home *** CD-ROM | disk | FTP | other *** search
- ; created 02/13/92
- ; updated 12/21/92
- ; revised 04/21/93 GETVOL$
- ; to display Norton Utilities Safe Format volume labels.
- ; NU routine ends a volume label with nulls rather than spaces.
- ; revised 04/22/93 SETVOL
- ; Test if drive is a network drive and quit if it is.
- ; revised 04/27/93 added DOS Ver 3.xx+ version information so could
- ; tell source of error. FCB functions return AX = 0FFh if drive
- ; is invalid and do not set any critical error. Only way to tell
- ; if access error or if drive is invalid is to use DOS Ver 3.xx+
- ; Function 59h.
- ; revised 04/30/93 SETVOL
- ; to handle Norton Utilities Safe Format.
- ; NU routine ends a volume label with nulls rather than spaces.
- ; Only function that will delete such a name is FCB function
- ; 13h. However, that function is not safe to use
- ; in DOS Version 2.xx. DOS Version 2.xx marked deleted volume
- ; label with 00h rather than correct 0E5h which prevented access
- ; to rest of directory list. Function 13h in MS DOS Version 5.00,
- ; 3.30, and COMPAQ DOS version 3.00 does not have this problem.
- ; Also add check of input string for invalid characters
-
- ;=======================================================================
- ; Modifications Copyright (C) Copr. 1992, 1993 by Sidney J. Kelly
- ; All Rights Reserved.
- ; Sidney J. Kelly
- ; 150 Woodhaven Drive
- ; Pittsburgh, PA 15228
- ; home phone 412-561-0950 (7pm to 9:30pm EST)
- ;=======================================================================
- ; «RM82»«TS8,16,24,32,40,48»
-
- DOSSEG
- .MODEL MEDIUM
-
- EXTRN B$ASSN:FAR ;This allows QBASIC to manipulate fixed length string
- EXTRN B$STDL:FAR ;This creates null strings
-
- .DATA
- EXTRN B$STRINGLEN:WORD ;inside FDATA
- EXTRN B$STRINGOFF:WORD ;inside FDATA
- EXTRN B$TEMPDATA:WORD ;inside FDATA
- ; this works inside QB as well as in run time version
- EXTRN __osversion :word;this holds minor version in highbyte,
- ;major version in lowbyte
- .CODE
-
- Public GETVOL, SETVOL
- ; Please do not remove
- Copyright DB 13,10,'Copyright Copr. (C) 1992, 1993 Sidney J. Kelly',13,10
- Copyright1 DB 'All Rights Reserved',13,10,26
-
- EVEN ;save space in DGROUP
- Old_CE Label DWORD
- CE_Off DW 0 ; to save space in DGROUP
- CE_Seg DW 0 ; address of previous handler
- Old_DTA Label DWORD
- DTA_Off DW 0 ; to save space in DGROUP
- DTA_Seg DW 0 ; address of previous handler
- Last_Error DW 0 ; store critical error code
-
- ; Format of an extended FCB---------------
- XFCB DB 0FFh ; signal XFCB
- DB 5 Dup(0) ; reserved DOS stuff
- DB 8 ; volume attribute
- Drive DB 0 ; drive code goes here
- FLabel DB 11 Dup(0) ; Volume name
- FExtra DB 5 Dup(0) ; reserved DOS stuff
- FNew DB 11 Dup(0) ; holding area for renaming
- FScrap DB 15 Dup(0) ; extra stuff and padding (6) extra
- ; Duncan, "Advanced MS DOS Programming" (Microsoft 1988), p366
- ; "Microsoft MS-DOS Programmer's Reference Guide" (Microsoft 1991)
-
- ;=======================================================================
- ; DECLARE FUNCTION GETVOL$(Drive$, DosErr%)
- ; T$ = GETVOL$(Drive$, DosErr%)
- ; Purpose:
- ; Returns current volume label of Drive$
- ; Input:
- ; Drive$ = Drive letter between 'A' to 'Z'. If out-of-range then
- ; default drive is substituted
- ; Output:
- ; T$ = the volume label. Note that volume labels can contain spaces.
- ; If any error encountered, returns NULL string
- ; DosErr:
- ; 0 if no critical error
- ; -1 if FCB error in DOS version 2.xx
- ; -2 if DOS Version 4.xx w/o SHARE
- ; Else
- ; Standard DOS errors from function 59h
- ; 18 = Drive has no label
- ; 21 = Drive not ready
- ; Theory:
- ; FCB's are used because they work under DOS version 2.x and they
- ; report the name without putting a period between the first
- ; 8 letters and the last 3 or squeezing out all the spaces.
- ;
- ; Note:
- ; Under DOS Ver 4.00, if SHARE is not loaded, then will return with
- ; a null string to prevent corruption of a large partition by reason of
- ; the use of FCBs.
- ;
- ; If drive is not valid, returns a null string and an error code.
- ;
- ; Has own critical error handler.
- ;=======================================================================
-
- DrvStrg EQU [BP+8] ; mnemonic for programmer
- DosErr EQU [BP+6]
-
- EVEN
- GETVOL PROC FAR
- Push BP
- Mov BP,SP ; get access to stack via BP
- Push SI ; save index registers
- Push DI ; ditto
- ; Mov AH,30h ; do a DOS version check
- ; Int 21h
- Mov AX,__osversion ; faster than above
- Cmp AL,4 ; DOS version 4.xx
- Jne @f ; not version 4.xx so skip ahead
- Mov AX,1000h ; else, (AL must = 0)
- Int 2Fh ; see if SHARE installed
- Cmp AL,0FFh ; if AL = FFh then it is installed
- Je @f ; o.k. to continue
- Mov CS:[Last_Error],-2 ; report DOS Ver 4.0x w/o SHARE
- Jmp Short Error ; else, return null string, error
- @@:
- ;Install CE Handler, trashes AX,BX,ES,DX, returns AX = @data
- Call CE_INSTALL
- Mov BX,DrvStrg ; get DRIVE$
- Mov CX,[BX] ; get length in CX
- JCXZ Use_Default ; if LEN(Drive$) = 0 use default drive
- Mov BX,[BX+2] ; get offset of string
- Mov AL,[BX] ; get character in AL
- And AL,0DFh ; capitalize character
- Sub AL,'@' ; make it 1 biased
- Or AL,AL ; is it 0?
- Jz Begin ; yes, so use default drive
- Cmp AL,27 ; is it > 26?
- JB Begin ; no, so test it
- Use_Default:
- Mov AH,19h ; else read default drive
- Int 21h ; into AL (useful for testing)
- Begin:
- ; AL must contain desired drive
- Call Search_4_Name ; search for current volume name
- ; must preserve DI because will use it below
- Assume DS:NOTHING, ES:NOTHING ; tell MASM
- Cmp AL,0FFh ; name found?
- Jne @f ; yes, so check for CE errors
- Call GetErrInfo ; else find out why not found
- @@:
- Cmp CS:[Last_Error],0 ; did DOS give us an error?
- Jne Error ; got an error
- ; new version
- ; revised 04/21/93 to handle Norton Utilities Safe Format
- ; NU routine ends a volume label with nulls rather than spaces. While
- ; QBASIC PRINT function can display nul strings, other routines
- ; may trigger errors.
- Mov CX,11 ; else, search for trailing spaces
- Dec DI ; remove 1 char overrun from DI
- Mov BL,20h ; look for a space
- Search_4_End:
- Mov AL,ES:[DI] ; get character
- Cmp AL,BL ; is it a space?
- Je @f ; yes, jump ahead
- Or AL,AL ; is it a nul?
- Jne Loop_Exit ; no, have end of label
- @@:
- Dec DI ; reduce pointer by 1
- Loop Search_4_End ; loop CX times
- Loop_Exit:
- JCXZ Error ; all spaces/nuls if CX = 0
- ; copy our string to DGROUP buffer
- Mov DX,CX ; save length in DX temporarily
- Mov SI,OFFSET FLabel ; put source string in DS:SI
- Mov AX,SS
- Mov ES,AX
- ; Assume ES:@data
- Assume DS:@data ; lie for a moment
- Mov DI,OFFSET B$TEMPDATA ; put destination in ES:DI
- Assume DS:NOTHING ; tell the truth again
- Rep MovsB ; store all the bytes
- Mov CX,DX ; restore CX to original length
- CopyString:
- ; Reset CE Handler, trashes AX,DX, returns AX = @data
- ; Note: must preserve CX!
- Call Clean_Up ; restore CE and DTA info
- Assume DS:@data
- ; return string to BASIC
- Push DS ; Store the Data Segment
- Mov AX,OFFSET B$TEMPDATA
- Push AX ; Store offset of string
- Push CX ; Store LEN of string
- Push DS ; Store the Data Segment
- Mov AX,OFFSET B$STRINGLEN
- Push AX ; Store Descriptor of string
- Xor AX,AX ; tell Basic it is a variable string
- Push AX ; Store a 0
- Call B$ASSN ; copy string into BASIC space
- Finis:
- Mov BX,DosErr
- Mov AX,CS:[Last_Error]
- Mov [BX],AX ; report back any critical errors
- Mov AX,OFFSET B$STRINGLEN ; address of descriptor
- Pop DI ; restore registers used
- Pop SI
- Pop BP
- Ret 4 ; remove 2 parameters from stack
- Error:
- Mov AH,0Dh ; reset disk because of error
- Int 21h
- ; Reset CE handler, trashes AX,DX, returns AX = @data
- ; Reset DTA address, preserves CX
- Call Clean_Up
- Assume DS:@data ; point DS to @data
- ; return NULL string
- Mov AX,OFFSET B$STRINGLEN ; put address of
- Push AX ; descriptor in AX
- Call B$STDL ; make it a null string
- Xor AX,AX ; clear descriptor too
- Mov B$STRINGLEN,AX ; needed only for MASM strings
- Mov B$STRINGOFF,AX
- Jmp Short Finis
- GETVOL ENDP
-
-
- ;=======================================================================
- ; DECLARE FUNCTION SETVOL%(Drive$, NewName$)
- ; T% = SETVOL$(Drive$, NewName$)
- ;
- ; Theory:
- ; FCB's are used because they work under DOS version 2.x, and they
- ; report the name without putting a period between the first
- ; 8 letters and the last 3. The handle functions work only under
- ; DOS Ver. 3.x+, they do not display the volume name properly. In
- ; addition, FCB's must be used to change volume names, even with
- ; DOS version 3.x+.
- ; Duncan, "Advanced MS DOS Programming" (Microsoft 1988), p175
- ;
- ; Input:
- ; Drive$ = Drive letter between 'A to Z' if out-of-range then
- ; default drive is substituted
- ; NewName$
- ; If LEN(NewName$) = 0 then
- ; old label will be deleted and no new label will be substituted.
- ;
- ; Routine allows use of embedded spaces. However, other characters
- ; that are not permitted in filenames will cause the routine
- ; to report an error.
- ;
- ; Returns:
- ; 0 = Change Successful
- ; -1 = FCB error in DOS version 2.xx (not used here)
- ; -2 = DOS Version error, Ver 4.0x w/o SHARE
- ; -3 = DOS Version less than 3.xx
- ; -4 = Network Drive, no label possible
- ; -5 = Invalid characters in NewName$ (nothing else happens)
- ; Else
- ; Standard DOS errors from function 59h
- ; 21, 83 = Drive not ready
- ; 8 = Invalid characters in input string
- ; 82 = Directory full
- ;
- ; Note:
- ; Under DOS Ver 4.0x, if SHARE is not loaded, then will not change
- ; Volume label to prevent corruption of a large partition by reason of
- ; the use of FCBs.
- ;
- ; Partly based on a public domain routine by William Cravener (11/14/92)
- ;
- ; Has own critical error handler.
- ;=======================================================================
-
- DrvStrg EQU [BP+8] ; mnemonic for programmer
- NewName EQU [BP+6]
-
- EVEN
- Bad_DOS:
- Mov CX,-3 ; report DOS version < 3.xx
- Jmp Finis1 ; quit
- EVEN
- Error2: ; stepping stone
- Jmp Return_CE_Err
- EVEN
- DV_Error: ; report back have DOS Ver 4.00 w/o SHARE
- Mov CX,-2 ; that version req. SHARE
- Jmp Finis1 ; or FCB's will damage large disks
- EVEN
- SETVOL PROC FAR
- Push BP
- Mov BP,SP ; get access to stack via BP
- Push SI ; save index registers
- Push DI ; ditto
- CLD ; to be safe
- Mov BX,NewName ; get address of NewName in BX
- Call CHECK_STRING ; check for invalid characters
- Jnc @f ; all characters valid
- Mov CX,-5 ; at least 1 character is invalid
- Jmp Finis1 ; quit with an error
- @@:
- ; Mov AH,30h ; do a DOS version check
- ; Int 21h
- Mov AX,__osversion ; faster than above
- Cmp AL,2 ; if version < 3.xx, quit
- Je Bad_DOS
- Cmp AL,4 ; check if DOS version 4.xx
- Jne Skip_Share ; not version 4.xx so skip ahead
- Mov AX,1000h ; else, (AL must = 0)
- Int 2Fh ; see if SHARE installed
- Cmp AL,0FFh ; if AL = FFh then it is installed
- Jne DV_Error ; if DOS Ver 4.00 w/o SHARE quit w/ error
- Skip_Share:
- ; Install CE Handler, trashes AX,BX,ES,DX, returns AX = @data
- Call CE_INSTALL
- Mov BX,DrvStrg ; get DRIVE$
- Mov CX,[BX] ; get length in CX
- JCXZ Use_Default1 ; if LEN(Drive$) = 0 use default drive
- Mov BX,[BX+2] ; get offset of string
- Mov AL,[BX] ; get character in AL
- And AL,0DFh ; capitalize character
- Sub AL,'@' ; make it 1 biased
- Or AL,AL ; is it 0?
- Jz Check_Net ; yes, so use default drive
- Cmp AL,27 ; is it > 26?
- JB Check_Net ; no, so use it
- Use_Default1:
- Mov AH,19h ; read default drive
- Int 21h ; into AL (useful for testing)
- Check_Net: ; see if a network drive
- Push AX ; save drive letter in AX
- Mov BL,AL ; put drive letter in BL
- Mov AX,4409h ; requires DOS version 3.10+
- Xor DX,DX ; make sure DX is 0 (for version 3.00)
- Int 21h ; check if drive is remote/local
- Jc Read_Current_Vol ; assume not a network if get error
- Pop AX ; restore AX
- Test DH,00010000b ; see if bit 12 set in DX
- Jz Read_Current_Vol ; bit clear, drive is local
- Mov CX,-4 ; report back drive is a network drive
- Jmp Error1 ; and quit
- Read_Current_Vol: ; see if any previous Vol. name
- ; AL must contain desired drive
- Call Search_4_Name ; search for current volume name
- Assume DS:NOTHING, ES:NOTHING ; tell MASM
- Cmp CS:[Last_Error],0 ; did DOS give us an error?
- Jne Error2 ; got an error, quit (through stepping stone)
- Cmp AL,0FFh ; name not found?
- Je Make_New_Vol ; yes, so set new one
- ; and ignore all non-CE errors
- Delete_Old_Name:
- ;Drive letter already set as well as attribute byte
- ;This section deletes all volume labels using wildcard feature of
- ; function 13h. This is the only way to delete any nul terminated
- ; volume labels such as that created by Norton's Safe Format.
- ; MS-DOS's Ver 5.00 LABEL.EXE has the same problem with
- ; Norton's Safe Format volume labels but does not use this solution
- ; which is why it can't delete null terminated volume labels.
- ; However MS-DOS version 3.30 LABEL.COM and COMPAQ version 3.00
- ; LABEL.COM can rename nul terminated volume labels.
- Assume DS:NOTHING, ES:NOTHING ; tell MASM
- Mov DI,OFFSET FLabel ; get address of search buffer
- Mov AL,'?' ; load '?' char into AL
- Mov CX,11 ; set to load 11 "?"'s
- Rep StosB ; load FCB (ES:DI) search buffer w/ all "?"
- Xor AL,AL
- Mov DI,OFFSET FExtra ; clean out old area
- Mov CX,31 ; muddied by name search
- Rep StosB ; into area pointed by ES:DI
- Mov DX,OFFSET XFCB ; point DX to XFCB
- Mov AH,13h ; delete old volume name
- Int 21h ; (unsafe in version 2.xx!!)
- Cmp AL,0FFh ; any error?
- Jne @f ; no, jump ahead
- Call GetErrInfo ; else, get reason for error
- @@:
- Cmp CS:[Last_Error],0 ; read CE/DOS error information
- Jne Return_CE_Err ; quit if get such an error
- Make_New_Vol:
- Xor AL,AL
- Mov DI,OFFSET FExtra ; clean out old area
- Mov CX,31 ; muddied by name search
- Rep StosB ; into area pointed by ES:DI
- Mov DI,OFFSET FLabel ; get address of search buffer into DI
- Call Parse_Name ; Load NewName$ into buffer
- Assume DS:NOTHING ; tell MASM DS=CS
- Jc Ender ; if LEN(NewName$) = 0 then quit
- Mov DX,OFFSET XFCB ; get offset into DX
- Mov AH,16h ; create new volume name
- Int 21h ; set volume to new name
- Cmp AL,0FFh ; any error?
- Jne @f ; no, jump ahead
- Call GetErrInfo ; else, get reason for error
- @@:
- Cmp CS:[Last_Error],0 ; read CE/DOS error information
- Jne Return_CE_Err ; quit if get such an error
- Close_File: ; Close file we just created
- Mov DX,OFFSET XFCB ; get offset into DX
- Mov AH,10h ; close file
- Int 21h ; ignore all close errors
- ; but critical errors
- Cmp CS:[Last_Error],0 ; read CE error information
- Jne Return_CE_Err ; quit if get a CE error
- Ender: ; else,
- ; preserves CX and sets DS = @data
- Call Clean_Up ; restore DTA & CE vectors
- Xor CX,CX ; report back all o.k.
- Assume DS:@data
- Finis1:
- Mov AX,CX ; get result code back from CX
- Pop DI ; restore registers used
- Pop SI
- Pop BP
- Ret 4 ; remove 2 parameter from stack
- Return_CE_Err:
- Mov CX,CS:[Last_Error] ; else get critical error in CX
- Error1:
- Mov AH,0Dh ; reset disk because of error
- Int 21h
- ; preserves CX and sets DS = @data
- Call Clean_Up ; restore DTA & CE vectors
- Assume DS:@data
- Jmp Short Finis1
- SETVOL ENDP
-
- ;=======================================================================
- ; Installs the CE handler, made a subroutine to save space
- ; Trashes AX,BX,ES,DX, returns AX = @data. ES & DS = @data
- ;=======================================================================
-
- EVEN
- CE_INSTALL PROC NEAR
- Assume DS:NOTHING, ES:NOTHING ; tell MASM only CS & SS defined
- Xor AX,AX
- Mov CS:[Last_Error],AX ; clear last error
- CLI ; prevent interruption
- Mov AX,3524h ; use DOS to get current
- Int 21h ; address of the vector
- Mov CS:[CE_Off],BX ; address returned in ES:BX
- Mov CS:[CE_Seg],ES ; save for removal
- Mov AX,CS
- Mov DS,AX ; set DS = CS
- ;need this so offset is calculated with reference to
- ;CSEG rather than DGROUP
- Assume DS:NOTHING
- Mov DX,OFFSET CE ; get address of our MASM handler
- Mov AX,2524h ; tell DOS we're taking this vector
- Int 21h ; grab the vector
- STI ; allow interrupts again
- Mov AX,SS ; in QBASIC SS=DGROUP
- Mov DS,AX
- Assume DS:@data ; reset DS = to DGROUP
- Mov ES,AX ; Make ES = DGROUP
- ; Assume ES:@data ; tell MASM
- Ret
- CE_INSTALL ENDP
-
- ;=======================================================================
- ;CHECK_STRING
- ; Check Input String for Invalid Characters
- ; Input:
- ; DS:BX points to input string's descriptor
- ; Result:
- ; Sets Carry if input string contains invalid characters
- ; Clears Carry if input string is o.k.
- ; Assumes:
- ; CLD
- ; Preserves:
- ; ES,SI,DI
- ; Trashes:
- ; AX,BX,CX,DX
- ;=======================================================================
-
- Invalid_Char db 34,59,9,0 ; quote, semicolon, tab, and nul
- db "*?&^+/,\=[.]<|>(:)"
- ; This list is from MS-DOS version 5.00 instruction book,
- ; FCB's also will permit you to use "^&()" in a volume label.
- Len_IC EQU $-Invalid_Char ; calculates length of Invalid_Char string
-
- EVEN
- CHECK_STRING PROC NEAR
- Assume ES:NOTHING, DS:@data
- Push ES ; save register we will change
- Push SI
- Push DI
- Mov CX,[BX] ; get length of input string
- Jcxz CS_OK ; if zero, quit
- Mov SI,[BX+2] ; get offset of string in SI
- Mov BX,CX ; store length of input in BX
- Mov AL,32 ; check for a leading space
- Cmp AL,Byte Ptr [SI]
- Je CS_Error ; a leading space is illegal, quit w/ error
- Mov AX,CS
- Mov ES,AX ; point ES to CS
- Assume DS:NOTHING ; lie so offset works
- Mov DX,OFFSET Invalid_Char ; ES:DX points to Invalid_Char string
- Assume DS:@data ; tell truth again
- EVEN ; speed up loop
- CS_Check:
- Dec BX ; reduce counter
- JS CS_OK ; if less than zero, quit, no matches
- LodsB ; put DS:SI into AL
- Mov CX,Len_IC ; put length of check string
- Mov DI,DX ; reload offset of comparison string
- Repne Scasb ; find first match, loop CX times
- ; as long as AL <> ES:DI, ZF set if match found
- Jz CS_Error ; found a match, so note the error
- Jmp Short CS_Check ; start loop again
- CS_OK:
- CLC
- CS_Finis:
- Pop DI ; restore registers
- Pop SI
- Pop ES
- Ret
- CS_Error:
- STC
- Jmp CS_Finis
- CHECK_STRING ENDP
-
- ;=======================================================================
- ; Search_4_Name
- ; Searches for current volume name, if found loads up XFCB with name
- ; Input:
- ; Assumes AL has desired drive
- ; Returns:
- ; DI pointing 1 byte higher in memory than end of FCB extension area
- ; DS = CS = ES
- ; changes DTA. AL = 0 if successful, AL = FF if error
- ;=======================================================================
-
- EVEN
- Search_4_Name Proc Near
- Mov CS:[Drive],AL ; store drive
- Mov AH,2Fh ; get current FCB DTA
- Int 21h
- Mov CS:[DTA_Off],BX ; save DTA address
- Mov CS:[DTA_Seg],ES
- Mov AX,CS
- Mov DS,AX ; DS points to SEG of XFCB
- Mov ES,AX ; ES points to SEG of XFCB
- Assume DS:NOTHING, ES:NOTHING ; tell MASM
- Mov DI,OFFSET FLabel ; get address of search buffer
- Mov AL,'?' ; load '?' char into AL
- Mov CX,11 ; set to load 11 "?"'s
- Rep StosB ; load FCB (ES:DI) search buffer w/ all "?"
- Mov DX,OFFSET XFCB ; put DTA buffer offset into DX
- Mov AH,1Ah ; move FCB DTA (DS:DX) to our area
- Int 21h
- Mov DX,OFFSET XFCB ; put extended FCB offset in DX
- Mov AH,11h ; do Find First search for volume label
- Int 21h ; volume attribute already fixed
- Ret
- Search_4_Name Endp
-
- ;=======================================================================
- ;Parse_Name
- ; Takes NewName$ and puts it into buffer pointed by DI
- ; Assumes:
- ; ES = CS, ES:DI contain address of start of destination buffer
- ; Changes:
- ; AX,BX,CX,DS,SI,DI
- ; Returns:
- ; IF LEN(NewName$) = 0 THEN Carry set
- ;
- ; ELSE Carry clear
- ;
- ; AX,DS = CS, CX = 0, BX = LEN(NewName$)
- ;=======================================================================
-
- NewName EQU [BP+6]
-
- EVEN
- Parse_Name Proc Near
- Mov BX,DI ; save incoming offset in BX
- Assume DS:NOTHING
- Mov AL,20h ; load space char into AL
- Mov CX,11 ; load 11 " "'s
- Rep Stosb ; into area pointed by ES:DI
- Mov DI,BX ; restore original value from BX
- Mov AX,SS
- Mov DS,AX
- Assume DS:@data ; get access to stack
- Mov SI,NewName
- Mov CX,[SI] ; get length in CX
- JCXZ Ender1 ; if LEN(NewName$) = 0 quit w/o error
- Mov SI,[SI+2] ; get offset of NewName$ into SI
- Mov BX,11 ; assume CX > 11 bytes
- Cmp CX,11 ; is LEN(NewName$) > 11
- Ja @f ; yes, so guessed correctly
- Mov BX,CX ; no, put actual LEN in BX
- @@:
- Mov CX,BX ; put min of old CX or 11 in CX
- Rep Movsb ; move DS:SI to ES:DI
- CLC ; clear carry flag
- Mov AX,CS
- Mov DS,AX ; reset DS to above buffer
- Assume DS:Nothing
- Ret
- Ender1:
- Mov BX,CX ; put 0 in BX
- Mov AX,CS
- Mov DS,AX ; reset DS to above buffer
- Assume DS:Nothing
- STC ; set carry flag
- Ret
- Parse_Name ENDP
-
- ;=======================================================================
- ; Clean_Up
- ; Resets CE handler, restores FCB DTA
- ; Sets AX & DS = @data
- ; Trashes DX. Saves CX
- ;=======================================================================
-
- EVEN
- Clean_Up PROC NEAR
- ; Reset CE handler, trashes AX,DX, returns AX = @data
- LDS DX,CS:[Old_CE] ; LDS is fast
- Assume DS:NOTHING
- Mov AX,2524h ; Restore 24h vector
- Int 21h ; restore it
- LDS DX,CS:[Old_DTA] ; LDS is fast
- Mov AH,1Ah ; Restore DTA area (DS:DX)
- Int 21h
- Mov AX,SS
- Mov DS,AX
- Assume DS:@data ; point DS to @data
- Ret
- Clean_Up ENDP
-
- ;=======================================================================
- ; GetErrInfo
- ; Purpose:
- ; Gets DOS's reason for FCB access error. If CE error already
- ; occurred, then CE error used. This prevents a "drive not ready" error
- ; (Code 21) from being converted into a "fail on interrupt 24h" (Code 83).
- ; Requires:
- ; DOS Version 3.00, returns FCB error of -1 if DOS version 2.xx
- ; Registers:
- ; All but AX and FLAGS are saved
- ;=======================================================================
-
- EVEN
- GetErrInfo PROC NEAR
- Assume DS:NOTHING, ES:NOTHING, SS:@data
- Mov AX,SS:[__osversion] ; check DOS version
- Cmp AL,2 ; DOS version 2.xx?
- Je Wrong_Ver ; quit, this function not supported in Ver 2.xx
- Cmp CS:[Last_Error],0 ; already have CE error? CS <> 0?
- Jne GetErrEnd ; yes, so use it
- Push BX ; save all important registers
- Push CX ; Function 59h destroys most registers
- Push DX
- Push SI
- Push DI
- Push BP
- Push DS
- Push ES
- Mov AH,59h ; call extended error information
- Xor BX,BX ; set implementation to 0
- Int 21h
- Mov CS:[Last_Error],AX ; store error code from AX
- Pop ES ; restore all registers changed
- Pop DS
- Pop BP
- Pop DI
- Pop SI
- Pop DX
- Pop CX
- Pop BX
- GetErrEnd: ; exit if CE handler already
- Ret ; got an error
- Wrong_Ver:
- Mov CS:[Last_Error],-1 ; store error code from AX
- Ret
- GetErrInfo ENDP
-
- ;=======================================================================
- ; Substitute critical error handler, does nothing but capture error.
- ; We let DOS process error, because that is only way to safely reset
- ; DOS's internal critical error flag.
- ;
- ; List of Critical errors:
- ; 19 = Disk write protected
- ; 20 = Unknown unit
- ; 21 = Drive not ready
- ; 22 = Unknown command
- ; 23 = CRC error
- ; 24 = Bad request structure length
- ; 25 = Seek error
- ; 26 = Unknown media type
- ; 27 = Sector not found
- ; 28 = Out of paper
- ; 29 = Write fault
- ; 30 = Read fault
- ; 31 = General failure
- ; 32 = Sharing violation
- ; 33 = Lock violation
- ; 34 = Invalid disk change
- ; 35 = FCB unavailable
- ; 36 = Sharing buffer overflow
- ;=======================================================================
-
- EVEN
- CE PROC FAR
- Assume DS:NOTHING, ES:NOTHING ; tell MASM only CS defined
- ;the following CODE returns to DOS for processing
- Add DI,13h ; increment error
- And DI,0FFh ; clear undefined portion
- Mov CS:[Last_Error],DI ; store in CSEG
- Xor AL,AL ; tell DOS to ignore error
- ; In DOS 3.xx and above, DOS will often turn ignore into fail
- ; which is what we want.
- IRET ; return & pop flags from stack
- CE ENDP
- END
-
-
- ;-----------------------------old code----------------------
-
- ;Rename_Old_Volume:
- ; We rename rather than delete using Function 13h because DOS Version 2.xx
- ; destroyed FAT if the volume label were erased. Rename function did not
- ; have that problem. Duncan, "Advanced MS DOS Programming"
- ; (Microsoft 1988), p175
- ;
- ; Rename DOES NOT permit a change to null terminated volume labels.
- ; therefore it was dropped.
- Assume DS:NOTHING, ES:NOTHING; tell MASM
- Mov DI,OFFSET FExtra ; clear out garbage
- Xor AL,AL ; put nul in AL
- Mov CX,5
- Rep StosB ; clean 5 spaces at ES:DI
- Mov DI,OFFSET FNew ; address of rename buffer into DI
- Call Parse_Name ; Load NewName$ into buffer
- Assume DS:NOTHING ; tell MASM DS=CS
- Jnc Do_Rename ; if no carry, then rename file
- ; else load a default name if LEN(NewName$) = 0
- Mov DI,OFFSET FNew ; else, LEN(NewName$) = 0
- Mov AL,'_' ; so give a default name of '_________'
- Mov CX,11
- Rep Stosb
- Do_Rename:
- Mov DX,OFFSET XFCB ; point to modified FCB
- Mov AH,17h ; rename it
- Int 21h
- Cmp AL,0FFh ; any error?
- Jne @f ; no, jump ahead
- Call GetErrInfo ; else, get reason for error
- @@:
- Cmp CS:[Last_Error],0 ; see if CE or DOS error
- Jne Return_CE_Err ; quit w/ CE/DOS error
- Jmp Close_File ; else, close file
-